home *** CD-ROM | disk | FTP | other *** search
/ Language/OS - Multiplatform Resource Library / LANGUAGE OS.iso / prolog / brklyprl.lha / Comp / peephole.pl < prev    next >
Text File  |  1989-04-14  |  6KB  |  175 lines

  1.  
  2. /* Copyright (C) 1988, 1989 Herve' Touati, Aquarius Project, UC Berkeley */
  3.  
  4. /* Copyright Herve' Touati, Aquarius Project, UC Berkeley */
  5.  
  6. % Do peephole optimization of several kinds:
  7. %          (1) many special instruction sequences.
  8. %         (2) code generation for some built-ins.
  9. %         (3) allocate & deallocate instructions.
  10. %         (4) last instruction (proceed or execute).
  11. %         (5) customization of instructions.
  12.  
  13. peephole(Code, PCode, Link, MaxSize) :- 
  14.     peephole(Code, PCode, Link, no_alloc, MaxSize, no_dummy), !.
  15.  
  16. % The call/1 predicate must be an escape:
  17. peephole([call(call/1,_)|Code], PCode, Link, Alloc, M, D) :- !,
  18.     peephole([call/1|Code], PCode, Link, Alloc, M, D).
  19.  
  20. % Insert the allocate and deallocate instructions
  21. % and take care of the last instruction.
  22. peephole([call(G,0)], LastCode, Link, Alloc, M, D) :- !,
  23.     lastcode(Alloc, LastCode, [execute(G)|Link]).
  24. peephole([], LastCode, Link, Alloc, M, D) :- !,
  25.     lastcode(Alloc, LastCode, [proceed|Link]).
  26.  
  27. % Insert the correct allocate instruction:
  28. peephole([I|Code], PCode, Link, no_alloc, M, D) :-
  29.     alloc_needed(I), !,
  30.     alloc_instruction(M, PCode, C1),
  31.     peephole([I|Code], C1, Link, yes_alloc, M, D).
  32.  
  33. % Insert call to dummy procedure if using old allocate instruction:
  34. % Must be done if 'try' or call/1 occurs as first call.
  35. % This is needed to initialize the N register.
  36. peephole([I|Code], PCode, Link, yes_alloc, M, D) :-
  37.     D=no_dummy,
  38.     compile_options(a),
  39.     not(compile_options(s)),
  40.     (I=..[try|_]; I=call/1), !,
  41.     load_nregister(M, PCode, [I|C1]),
  42.     peephole(Code, C1, Link, yes_alloc, M, yes_dummy).
  43.  
  44. % Recognize and eliminate superfluous jumps:
  45. peephole([label(Lbl),execute(Lbl)|Code], 
  46.      [execute(Lbl)|PCode], Link, Alloc, M, D) :- !,
  47.     peephole(Code, PCode, Link, Alloc, M, D).
  48.  
  49. % Remove all code after a fail/0 until reaching a
  50. % label, retry, or trust:
  51. % (calls to peephole and f_remove must be in this order for best working!)
  52. peephole([fail/0|Code], [fail/0|PCode], Link, Alloc, M, D) :- !,
  53.     peephole(Code, MCode, Link, Alloc, M, D),
  54.     f_remove(MCode, PCode).
  55.  
  56. % Finishing touches for VLSI PLM arithmetic instructions:
  57. % peephole(Code, PCode, Link, Alloc, M, D) :-
  58. %     Code=[put(T1,X,x(I)),put(T2,Y,x(J)),Instr,get(T3,Z,x(J))|C1],
  59. %     (var(I); var(J)),
  60. %     Instr=..[Opcode|_], vlsi_instr(_, Opcode),
  61. %     % (Z=x(J); true),
  62. %     (Y=x(J); true),
  63. %     (X=x(I); true),
  64. %     (I=8; true),
  65. %     (J=8; true), I\==J,
  66. %     peephole(Code, PCode, Link, Alloc, M, D).
  67.  
  68. % Optimize unify goals:
  69. % First case: one variable is temporary or void:
  70. peephole([put(variable,R,R),get(A,X,R)|Code], PCode, Link, Alloc, M, D) :-
  71.     R=x(I),
  72.     integer(I), !,
  73.     peephole([put(A,X,R)|Code], PCode, Link, Alloc, M, D).
  74. % Second case: both variables are permanent:
  75. % What if X==Y???
  76. peephole([put(A,X,x(8)),get(B,Y,x(8))|Code], PCode, Link, Alloc, M, D) :-
  77.     X\==Y, X=y(N1), Y=y(N2), !,
  78.     update_unsafe(A, B, NewA, NewB),
  79.     PCode=[put(NewA,X,x(8)),get(NewB,Y,x(8))|MCode],
  80.     peephole(Code, MCode, Link, Alloc, M, D).
  81.  
  82. % Optimize unify_cdr:
  83. peephole([unify(cdr,x(8)),get(variable,X,x(8))|Code], PCode, Link, Alloc, M, D) :- !,
  84.     peephole([unify(cdr,X)|Code], PCode, Link, Alloc, M, D).
  85. peephole([unify(cdr,x(8)),get(unsafe_value,X,x(8))|Code],
  86.      [unify(cdr,x(8)),get(value,X,x(8))|PCode], Link, Alloc, M, D) :- !,
  87.     peephole(Code, PCode, Link, Alloc, M, D).
  88.  
  89. % Remove superfluous initializations of permanent variables:
  90. peephole([put(value,y(_),x(8)),I|Code], PCode, Link, Alloc, M, D) :-
  91.     I=..[Name|_], Name\==get, !,
  92.     peephole([I|Code], PCode, Link, Alloc, M, D).
  93.  
  94. % Remove no-op register transfers:
  95. peephole([I|Code], PCode, Link, Alloc, M, D) :-
  96.     (I=get(variable,R,R); I=put(value,R,R); I=get(value,R,R)),
  97.     R=x(_), !,
  98.     peephole(Code, PCode, Link, Alloc, M, D).
  99.  
  100. % Remove remaining unsafe_values
  101. peephole([get(unsafe_value,A,B)|Code], [get(value,A,B)|PCode], Link, Alloc, M, D) :- !,
  102.     peephole(Code, PCode, Link, Alloc, M, D).
  103.  
  104. % Post-transformation: 
  105. % Generates code for some built-ins in terms of 
  106. % existing instructions.
  107. peephole([Name/Arity|Code], PCode, Link, Alloc, M, D) :-
  108.     post_trans(Name, Arity, TCode-Code), !,
  109.     peephole(TCode, PCode, Link, Alloc, M, D).
  110.  
  111. % Customization of instructions:
  112. peephole([I|Code], [CI|PCode], Link, Alloc, M, D) :-
  113.     customize(I, CI), !,
  114.     peephole(Code, PCode, Link, Alloc, M, D).
  115.  
  116. % Default:
  117. peephole([I|Code], [I|PCode], Link, Alloc, M, D) :-
  118.     peephole(Code, PCode, Link, Alloc, M, D).
  119.  
  120. % Update unsafe_value annotations of put-get sequence:
  121. update_unsafe(A, unsafe_value, A, value) :- !.
  122. update_unsafe(unsafe_value, B, value, B) :- !.
  123. update_unsafe(A, B, A, B) :- !.
  124.  
  125. % Remove code until encountering a
  126. % label, retry, or trust:
  127. f_remove([], []).
  128. f_remove([Instr|Code], [Instr|Code]) :-
  129.     Instr=..[N|_],
  130.     (N=label; N=retry; N=trust), !.
  131. f_remove([_|Code], RCode) :-
  132.     f_remove(Code, RCode).
  133.  
  134. % Table of builtins with code:
  135. post_trans(var, 1, [switch_on_term(fail,fail,fail)|L]-L).
  136. post_trans(nonvar, 1, [switch_on_term(Lbl,Lbl,Lbl),fail/0,label(Lbl)|L]-L).
  137. post_trans(atomic, 1, [switch_on_term(Lbl,fail,fail),fail/0,label(Lbl)|L]-L).
  138. post_trans(nonatomic, 1, [switch_on_term(fail,Lbl,Lbl),label(Lbl)|L]-L).
  139. post_trans(list, 1, [switch_on_term(fail,Lbl,fail),fail/0,label(Lbl)|L]-L).
  140. post_trans(nonlist, 1, [switch_on_term(Lbl,fail,Lbl),label(Lbl)|L]-L).
  141. post_trans(structure, 1, [switch_on_term(fail,fail,Lbl),fail/0,label(Lbl)|L]-L).
  142. post_trans(composite, 1, [switch_on_term(fail,Lbl,Lbl),fail/0,label(Lbl)|L]-L).
  143. post_trans(simple, 1, [switch_on_term(Lbl,fail,fail),label(Lbl)|L]-L).
  144. post_trans(repeat, 0, [try(Lbl),label(Lbl)|L]-L).
  145.  
  146. % Customize one instruction:
  147. customize(get(structure,'.'/2,B), get_list(B)).
  148. customize(put(structure,'.'/2,B), put_list(B)).
  149. customize(put(constant,[],A), put_nil(A)).
  150. customize(get(constant,[],A), get_nil(A)).
  151.  
  152. % Succeeds if an allocate instruction is needed
  153. % before instruction I:
  154. alloc_needed(I) :-
  155.     I =..[call|_].
  156. %    I=..[Name|_],
  157. %    (Name=call;Name=try;Name=cut).
  158. alloc_needed(I) :-
  159.     (I=get(_,V,_);I=put(_,V,_);I=unify(_,V)),
  160.     nonvar(V), V=y(_).
  161.  
  162. % No Need to have a deallocate instruction any more:
  163. lastcode(yes_alloc, L, L).
  164. lastcode(no_alloc,  L, L).
  165.  
  166. % The allocate instruction:
  167. alloc_instruction(M, [allocate,loadn(M)|Link], Link) :-
  168.     compile_options(s), !.
  169. alloc_instruction(M, [allocate|Link], Link) :-
  170.     compile_options(a), !.
  171. alloc_instruction(M, [allocate(M)|Link], Link).
  172.  
  173. % Loading the N register:
  174. load_nregister(M, [call(allocate_dummy/0,M)|Link], Link).
  175.